home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / smaltalk / gnu_st.lha / gnu_st / smalltalk-1.1.1 / Set.st < prev    next >
Text File  |  1991-09-12  |  7KB  |  254 lines

  1. "======================================================================
  2. |
  3. |   Set Method Definitions
  4. |
  5.  ======================================================================"
  6.  
  7.  
  8. "======================================================================
  9. |
  10. | Copyright (C) 1990, 1991 Free Software Foundation, Inc.
  11. | Written by Steve Byrne.
  12. |
  13. | This file is part of GNU Smalltalk.
  14. |
  15. | GNU Smalltalk is free software; you can redistribute it and/or modify it
  16. | under the terms of the GNU General Public License as published by the Free
  17. | Software Foundation; either version 1, or (at your option) any later version.
  18. | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT
  19. | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
  20. | FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
  21. | details.
  22. | You should have received a copy of the GNU General Public License along with
  23. | GNU Smalltalk; see the file COPYING.  If not, write to the Free Software
  24. | Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.  
  25. |
  26.  ======================================================================"
  27.  
  28.  
  29. "
  30. |     Change Log
  31. | ============================================================================
  32. | Author       Date       Change 
  33. | sbyrne     19 Sep 89      Converted to use real method categories.
  34. |
  35. | sbyrne     25 Apr 89      created.
  36. |
  37. "
  38.  
  39. Collection variableSubclass: #Set
  40.        instanceVariableNames: 'tally'
  41.        classVariableNames: ''
  42.        poolDictionaries: ''
  43.        category: nil.
  44.  
  45. Set comment:
  46. 'I am the typical set object; I can store any objects uniquely.  I
  47. use the = operator to determine duplication of objects.' !
  48.  
  49. !Set class methodsFor: 'instance creation'!
  50.  
  51. new
  52.     ^self new: 4
  53. !
  54.  
  55. new: anInteger
  56.     ^(super new: anInteger) setTally
  57. !!
  58.  
  59.  
  60.  
  61. !Set methodsFor: 'accessing'!
  62.  
  63. at: index
  64.     self error: 'at: not allowed for Set'
  65. !
  66.  
  67. at: index put: value
  68.     self error: 'at:put: not allowed for Set'
  69. !
  70.  
  71. add: newObject
  72.     | index |
  73.     newObject isNil ifTrue: [ ^newObject ].
  74.     index _ self findObjectIndex: newObject.
  75.     (self basicAt: index) isNil
  76.         ifTrue: [ self basicAt: index put: newObject.
  77.               tally _ tally + 1 ].
  78.     ^newObject
  79. !!
  80.  
  81.  
  82.  
  83. !Set methodsFor: 'Removing from a collection'!
  84.  
  85. remove: oldObject ifAbsent: anExceptionBlock
  86.     | index |
  87.     index _ self findObjectIndexNoGrow: oldObject
  88.                  ifAbsent: [ ^anExceptionBlock value ].
  89.     tally _ tally - 1.
  90.     self rehashObjectsAfter: index.
  91.     ^oldObject
  92. !!
  93.  
  94.  
  95.  
  96. !Set methodsFor: 'testing collections'!
  97.  
  98. includes: anObject
  99.     ^(self basicAt: (self findObjectIndex: anObject)) ~~ nil
  100. !
  101.  
  102. isEmpty
  103.     ^tally == 0
  104. !
  105.  
  106. occurrencesOf: anObject
  107.     "Return the number of occurrences of anObject.  Since we're a set, this
  108.     is either 0 or 1.  Nil is never directly in the set, so we special case
  109.     it here."
  110.     anObject isNil ifTrue: [ ^1 ].
  111.     (self includes: anObject)
  112.         ifTrue: [ ^1 ]
  113.     ifFalse: [ ^0 ]
  114. !
  115.  
  116. size
  117.     ^tally
  118. !
  119.  
  120. hash
  121.     "Return the hash code for the members of the set.  Since order is
  122.     unimportant; we use a commutative operator to compute the hash value."
  123.     ^self inject: tally
  124.           into: [ :hashValue :member | hashValue + member hash ]
  125. !
  126.  
  127. = aSet
  128.     "Returns true if the two sets have the same membership, false if not"
  129.     tally = aSet size  ifFalse: [ ^false ].
  130.     self do: [ :element | (aSet includes: element)
  131.                             ifFalse: [ ^false ] ].
  132.     ^true
  133. !!
  134.  
  135.  
  136.  
  137. !Set methodsFor: 'enumerating the elements of a collection'!
  138.  
  139. do: aBlock
  140.     "Enumerate all the non-nil members of the set"
  141.     1 to: self basicSize do:
  142.         [ :i | (self basicAt: i) notNil
  143.               ifTrue: [ aBlock value: (self basicAt: i) ] ]
  144. !!
  145.  
  146.  
  147.  
  148. !Set methodsFor: 'printing'!
  149.  
  150. printOn: aStream
  151.     | firstTime |
  152.     aStream nextPutAll: self class name , ' ('.
  153.     firstTime _ true.
  154.     self do:
  155.         [ :element | firstTime ifTrue: [ firstTime _ false ]
  156.                            ifFalse: [ aStream nextPutAll: ' ' ].
  157.              element storeOn: aStream ].
  158.     aStream nextPut: $).
  159. !!
  160.  
  161.  
  162.  
  163. !Set methodsFor: 'storing'!
  164.  
  165. storeOn: aStream
  166.     | hasElements |
  167.     aStream nextPutAll: '(Set new'.
  168.     hasElements _ false.
  169.     self do:
  170.         [ :element | aStream nextPutAll: ' add: '.
  171.              element storeOn: aStream.
  172.              aStream nextPut: $;.
  173.              hasElements _ true ].
  174.     hasElements ifTrue: [ aStream nextPutAll: ' yourself' ].
  175.     aStream nextPut: $).
  176. !!
  177.  
  178.  
  179.  
  180. !Set methodsFor: 'private methods'!
  181.  
  182. setTally
  183.     "Instance variable initialization."
  184.     tally _ 0
  185. !
  186.  
  187. rehashObjectsAfter: index
  188.     "Rehashes all the objects in the collection after index to see if any of
  189.     them hash to index.  If so, that object is copied to index, and the
  190.     process repeats with that object's index, until a nil is encountered."
  191.     | i size count element |
  192.     i _ index.
  193.     size _ self basicSize.
  194.     count _ size.
  195.     self basicAt: index put: nil.
  196.     [ count _ count - 1.
  197.       i _ i \\ size + 1.
  198.       element _ self basicAt: i.
  199.       count > 0 and: [ element notNil ] ]
  200.         whileTrue:
  201.         [ self basicAt: i put: nil.
  202.           self basicAt: (self findObjectIndex: element) put: element ].
  203.     ^self
  204. !
  205.  
  206. findObjectIndex: anObject ifFull: aBlock
  207.     "Tries to see if anObject exists as an indexed variable.  If it's searched
  208.     the entire set and the object is not to be found, aBlock is evaluated and
  209.     it's value is returned."
  210.     | index count size newSet element |
  211.     size _ self basicSize.
  212.     index _ anObject hash \\ size + 1.
  213.     count _ size.
  214.     [ count > 0 ]
  215.         whileTrue:
  216.         [ element _ self basicAt: index.
  217.               (element isNil or: [ element = anObject ])
  218.             ifTrue: [ ^index ].
  219.           index _ index \\ size + 1.
  220.           count _ count - 1 ].
  221.     ^aBlock value
  222. !
  223.         
  224. findObjectIndex: anObject
  225.     "Finds the given object in the set and returns its index.  If the set
  226.     doesn't contain the object and there is no nil element, the set is
  227.     grown and then the index of where the object would go is returned."
  228.     ^self findObjectIndex: anObject
  229.            ifFull: [ self grow.
  230.                 self findObjectIndexNoGrow: anObject
  231.                     ifAbsent: [ self error: 'failed to grow a new empty element!!!' ] ]
  232. !
  233.  
  234. findObjectIndexNoGrow: anObject ifAbsent: aBlock
  235.     | index |
  236.     index _ self findObjectIndex: anObject ifFull: [ 0 ].
  237.     index = 0 
  238.         ifTrue: [ ^aBlock value ]
  239.     ifFalse: [ ^index ]
  240. !
  241.  
  242. grow
  243.     | newSet |
  244.     newSet _ self species new: self basicSize + self growSize.
  245.     self do: [ :element | newSet add: element ].
  246.     ^self become: newSet
  247. !
  248.  
  249. growSize
  250.     ^self basicSize        "this will double the size"
  251. !!
  252.